home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / sbprolog / v3 / modlib_s.lha / modlib_src / $currsym.P < prev    next >
Text File  |  1990-04-12  |  8KB  |  286 lines

  1. /************************************************************************
  2. *                                    *
  3. * The SB-Prolog System                            *
  4. * Copyright SUNY at Stony Brook, 1986; University of Arizona,1987    *
  5. *                                    *
  6. ************************************************************************/
  7.  
  8. /*-----------------------------------------------------------------
  9. SB-Prolog is distributed in the hope that it will be useful,
  10. but WITHOUT ANY WARRANTY.  No author or distributor
  11. accepts responsibility to anyone for the consequences of using it
  12. or for whether it serves any particular purpose or works at all,
  13. unless he says so in writing.  Refer to the SB-Prolog General Public
  14. License for full details.
  15.  
  16. Everyone is granted permission to copy, modify and redistribute
  17. SB-Prolog, but only under the conditions described in the
  18. SB-Prolog General Public License.   A copy of this license is
  19. supposed to have been given to you along with SB-Prolog so you
  20. can know your rights and responsibilities.  It should be in a
  21. file named COPYING.  Among other things, the copyright notice
  22. and this notice must be preserved on all copies. 
  23. ------------------------------------------------------------------ */
  24.  
  25. $currsym_export([$current_predicate/2,$current_predicate/3,$predicate_property/2,
  26.          $predicate_property/3, $current_functor/2,
  27.          $current_functor/3,$current_atom/1,$current_atom/2]).
  28.  
  29. $currsym_use($buff, [_,_,_,_,$symtype/2,_,_,_,_,_,_]).
  30. $currsym_use($bmeta,[$atom/1,_,_,_,_,$functor0/2,_,_,_,_,_,$mkstr/3,_]).
  31.  
  32.  
  33. $current_predicate(X,Y) :- $current_predicate(X,Y,_,0).
  34. $current_predicate(X,Y,ShowAll) :- $current_predicate(X,Y,_,ShowAll).
  35.  
  36. $predicate_property(Pred,Prop) :- $predicate_property(Pred,Prop,0).
  37.  
  38. $predicate_property(Pred,interpreted,ShowAll) :-
  39.      $current_predicate(_,Pred,1,ShowAll).
  40. $predicate_property(Pred,compiled,ShowAll) :- 
  41.      $current_predicate(_,Pred,2,ShowAll).
  42.  
  43. $current_predicate(X,Y,Type,ShowAll) :-
  44.      (Type = 1 /* asserted */ ; Type = 2 /* compiled */ ),
  45.      (var(Y) ->
  46.           ($current_symbol(0,0,Type,0,X0,Y),
  47.        ((nonvar(X) ; ShowAll > 0) ->
  48.             true ;
  49.         ($external_symbol(X0), not($internal_pred(Y)))
  50.        ),
  51.        X0 = X
  52.           ) ;
  53.       ($symtype(Y, Type),
  54.        $functor0(Y,X)
  55.       )
  56.      ).
  57.  
  58. $current_functor(X,Y) :- $current_functor(X,Y,0).
  59.  
  60. $current_functor(X,Y,ShowAll) :-
  61.      $current_symbol(0,0,0,0,X0,Y0),
  62.      (ShowAll > 0 ->
  63.          true ;
  64.      $external_symbol(X0)
  65.      ),
  66.      X0 = X,
  67.      Y0 = Y.
  68. $current_functor(X,Y,ShowAll) :- $current_predicate(X,Y,ShowAll).
  69.  
  70. $current_atom(X) :- $current_atom(X,0).
  71.  
  72. $current_atom(X,ShowAll) :-
  73.      $current_symbol(0,0,0,0,X0,_),
  74.      (ShowAll > 0 ->
  75.          true ;
  76.      $external_symbol(X0)
  77.      ),
  78.      $atom(X0),
  79.      X = X0.
  80.  
  81. $current_symbol(CurrBucket,CurrElt,Type,OldP,X,Y) :-
  82.      $stlookup(CurrBucket,CurrElt,Type,OldP,NewBucket,NewElt,Psc),
  83.      (($mkstr(Psc,Y,_),
  84.        $functor0(Y,X)
  85.       ) ;
  86.       $current_symbol(NewBucket,NewElt,Type,1,X,Y)
  87.      ).
  88.  
  89. $stlookup(A,B,C,D,E,F,G) :- '_$builtin'(14).
  90.  
  91. /* a symbol is considered an external symbol if its name does not begin
  92.    with $ or _$.
  93. */
  94.  
  95. $external_symbol(X) :-
  96.      $name(X,Xname),
  97.      not( (Xname = [0'$ | _] ;
  98.            Xname = [0'_, 0'$|_]
  99.       )
  100.     ).
  101.  
  102. $internal_pred(define_mod(_,_)).
  103. $internal_pred(load(_)).
  104. $internal_pred(writename(_)).
  105. $internal_pred(writeqname(_)).
  106. $internal_pred(put(_)).
  107. $internal_pred(nl).
  108. $internal_pred(tab(_)).
  109. $internal_pred(tell(_)).
  110. $internal_pred(telling(_)).
  111. $internal_pred(told).
  112. $internal_pred(get(_)).
  113. $internal_pred(get0(_)).
  114. $internal_pred(see(_)).
  115. $internal_pred(seeing(_)).
  116. $internal_pred(seen).
  117. $internal_pred(write(_)).
  118. $internal_pred(writeq(_)).
  119. $internal_pred(display(_)).
  120. $internal_pred(print(_)).
  121. $internal_pred(print_al(_,_)).
  122. $internal_pred(print_ar(_,_)).
  123. $internal_pred(errmsg(_)).
  124. $internal_pred(assert(_)).
  125. $internal_pred(asserta(_)).
  126. $internal_pred(asserta(_,_)).
  127. $internal_pred(assertz(_)).
  128. $internal_pred(assertz(_,_)).
  129. $internal_pred(assert(_,_)).
  130. $internal_pred(asserti(_,_)).
  131. $internal_pred(assert(_,_,_,_)).
  132. $internal_pred(assert_union(_,_)).
  133. $internal_pred(atom(_)).
  134. $internal_pred(atomic(_)).
  135. $internal_pred(integer(_)).
  136. $internal_pred(number(_)).
  137. $internal_pred(structure(_)).
  138. $internal_pred(functor0(_,_)).
  139. $internal_pred(bldstr(_,_,_)).
  140. $internal_pred(arg(_,_,_)).
  141. $internal_pred(arity(_,_)).
  142. $internal_pred(real(_)).
  143. $internal_pred(float(_)).
  144. $internal_pred(is_buffer(_)).
  145. $internal_pred(functor(_,_,_)).
  146. $internal_pred('=..'(_,_)).
  147. $internal_pred(length(_,_)).
  148. $internal_pred(name(_,_)).
  149. $internal_pred(name0(_,_)).
  150. $internal_pred(read(_)).
  151. $internal_pred(read(_,_)).
  152. $internal_pred('='(_,_)).
  153. $internal_pred('<'(_,_)).
  154. $internal_pred('=<'(_,_)).
  155. $internal_pred('>='(_,_)).
  156. $internal_pred('>'(_,_)).
  157. $internal_pred('=:='(_,_)).
  158. $internal_pred('=\='(_,_)).
  159. $internal_pred(is(_,_)).
  160. $internal_pred(eval(_,_)).
  161. $internal_pred(var(_)).
  162. $internal_pred(nonvar(_)).
  163. $internal_pred(fail).
  164. $internal_pred(true).
  165. $internal_pred(halt).
  166. $internal_pred(repeat).
  167. $internal_pred(break).
  168. $internal_pred(abort).
  169. $internal_pred('?='(_,_)).
  170. $internal_pred('\='(_,_)).
  171. $internal_pred(cputime(_)).
  172. $internal_pred(syscall(_,_,_)).
  173. $internal_pred(system(_)).
  174. $internal_pred(globalset(_)).
  175. $internal_pred(gennum(_)).
  176. $internal_pred(gensym(_,_)).
  177. $internal_pred('=='(_,_)).
  178. $internal_pred('\=='(_,_)).
  179. $internal_pred('@=<'(_,_)).
  180. $internal_pred('@<'(_,_)).
  181. $internal_pred('@>'(_,_)).
  182. $internal_pred('@>='(_,_)).
  183. $internal_pred(compare(_,_,_)).
  184. $internal_pred(debug).
  185. $internal_pred(nodebug).
  186. $internal_pred(trace(_)).
  187. $internal_pred(untrace(_)).
  188. $internal_pred(spy(_)).
  189. $internal_pred(nospy(_)).
  190. $internal_pred(debugging).
  191. $internal_pred(tracepreds(_)).
  192. $internal_pred(spypreds(_)).
  193. $internal_pred(retract(_)).
  194. $internal_pred(abolish(_)).
  195. $internal_pred(abolish(_,_)).
  196. $internal_pred(retractall(_)).
  197. $internal_pred(consult(_)).
  198. $internal_pred(consult(_,_)).
  199. $internal_pred(consult(_,_,_)).
  200. $internal_pred(alloc_perm(_,_)).
  201. $internal_pred(alloc_heap(_,_)).
  202. $internal_pred(trimbuff(_,_,_)).
  203. $internal_pred(symtype(_,_)).
  204. $internal_pred(substring(_,_,_,_,_,_)).
  205. $internal_pred(subnumber(_,_,_,_,_,_)).
  206. $internal_pred(subdelim(_,_,_,_,_,_)).
  207. $internal_pred(conlength(_,_)).
  208. $internal_pred(pred_undefined(_)).
  209. $internal_pred(defint_call(_,_,_,_)).
  210. $internal_pred(setof(_,_,_)).
  211. $internal_pred(bagof(_,_,_)).
  212. $internal_pred(findall(_,_,_)).
  213. $internal_pred(sort(_,_)).
  214. $internal_pred(keysort(_,_)).
  215. $internal_pred(compile).
  216. $internal_pred(compile(_)).
  217. $internal_pred(compile(_,_)).
  218. $internal_pred(compile(_,_,_)).
  219. $internal_pred(compile(_,_,_,_)).
  220. $internal_pred(getclauses(_,_)).
  221. $internal_pred(getclauses(_,_,_)).
  222. $internal_pred(attach(_,_)).
  223. $internal_pred(expand_term(_,_)).
  224. $internal_pred(append(_,_,_)).
  225. $internal_pred(member(_,_)).
  226. $internal_pred(et(_)).
  227. $internal_pred(noet(_)).
  228. $internal_pred(et_star(_)).
  229. $internal_pred(et_points(_)).
  230. $internal_pred(et_remove(_)).
  231. $internal_pred(et_answers(_,_)).
  232. $internal_pred(et_calls(_,_)).
  233. $internal_pred(floatc(_,_,_)).
  234. $internal_pred(exp(_,_)).
  235. $internal_pred(square(_,_)).
  236. $internal_pred(sin(_,_)).
  237. $internal_pred(floor(_,_)).
  238. $internal_pred(count(_)).
  239. $internal_pred(time(_)).
  240. $internal_pred(nocount(_)).
  241. $internal_pred(notime(_)).
  242. $internal_pred(profiling).
  243. $internal_pred(prof_reset(_)).
  244. $internal_pred(resetcount(_)).
  245. $internal_pred(resettime(_)).
  246. $internal_pred(profile).
  247. $internal_pred(noprofile).
  248. $internal_pred(timepreds(_)).
  249. $internal_pred(countpreds(_)).
  250. $internal_pred(prof_stats(_)).
  251. $internal_pred(prof_stats).
  252. $internal_pred(statistics).
  253. $internal_pred(statistics(_,_)).
  254. $internal_pred(dcg(_,_)).
  255. $internal_pred(phrase(_,_)).
  256. $internal_pred(phrase(_,_,_)).
  257. $internal_pred(portray_term(_)).
  258. $internal_pred(portray_clause(_)).
  259. $internal_pred(clause(_,_)).
  260. $internal_pred(clause(_,_,_)).
  261. $internal_pred(listing(_)).
  262. $internal_pred(instance(_,_)).
  263. $internal_pred(listing).
  264. $internal_pred(erase(_)).
  265. $internal_pred(recorda(_,_,_)).
  266. $internal_pred(recordz(_,_,_)).
  267. $internal_pred(recorded(_,_,_)).
  268. $internal_pred(current_predicate(_,_)).
  269. $internal_pred(predicate_property(_,_)).
  270. $internal_pred(current_functor(_,_)).
  271. $internal_pred(current_atom(_)).
  272. $internal_pred(loaded_mods(_)).
  273. $internal_pred(defined_mods(_,_)).
  274. $internal_pred(call(_)).
  275. $internal_pred(','(_,_)).
  276. $internal_pred(','(_,_,_,_)).
  277. $internal_pred(';'(_,_)).
  278. $internal_pred(not(_)).
  279. $internal_pred('->'(_,_)).
  280. $internal_pred('\+'(_)).
  281. $internal_pred('$hashval'/3).
  282. $internal_pred(hashval/3).
  283.  
  284. /* ------------------------------ $currsyms.P ------------------------------ */
  285.  
  286.